home *** CD-ROM | disk | FTP | other *** search
- {$G+}
- program CDemo4;
- const
- NumPnts = 156;
- Xc = 0;
- Yc = 0;
- zc = 80;
- BlockMaxX = 15; { Horiz Size Of Block }
- BlockMaxY = 14; { Vert Size Of Block }
- NumSxhma = 6;
- MorphSize=20;
-
- VSeg : word =$A000;
- Sox : Word = 160;
- Soy : Word = 100;
- dist : Byte = 0;
-
- ScrText : string =
- ' COSMOS BBS - Katerini Greece (+30-351-37382) '#1' 21:00-9:00'+
- 'Gmt+2 - 2400 to Zyx16.8/V32bis '#2' HQ-Greece for Pascal-Net 115:3000/0 '+
- #1' Fidonet 2:410/204 '#2' SBC-Net 14:2100/201 '#1' ZyxelNet 16:800/108 '+
- #2' Hellas-Net 7:2000/50 '#1' ...call us now...';
- FinText : Array[1..7] of string[43] =
- ('─────══════─C─O─S─M─O─S───B─B─S─══════─────',
- ' Katerini, HELLAS 2:410/204 Fidonet ',
- ' +30-351-37382 115:3005/1 Pascal-Net',
- ' Zyxel 16.8/V32Bis 14:2100/201 SBC-Net ',
- ' 7:2000/50 HellasNet ',
- 'Weekdays 21:00-09:00, Sat-Sun 24Hrs (Gmt+2)',
- ' SysOp: Sokrates Passalidis ');
-
- Type
- VGAPtr = ^VGAType;
- PaletteRec = Record R,G,B : Byte; End;
- PaletteType = Array[0..255] of PaletteRec;
- TabType = array[0..255] of integer;
- PointArray = Array[1..NumPnts,1..3] of ShortInt;
- BlockArray = Array [0..BlockMaxY-1, 0..BlockMaxX-1] of Byte;
- VGAType = Array[0..199, 0..319] of Byte;
- SxhmataTyp = Array[0..NumSxhma-1] OF PointArray;
- MArrTyp = PointArray;
- TxtBMap = Array[0..7,0..2048] OF byte;
-
-
-
- var
- Fseg,Fofs : word;
- VGA : VGAPtr;
- Block : ^BlockArray;
- BlockPal : ^PaletteType;
- SinTab : ^TabType;
- Sxhmata : ^SxhmataTyp;
- MArr : ^MarrTyp;
- PA1 : ^PointArray;
- TxtBit : TxtBMap;
- Cover : Array[0..320*8] of byte;
- I : Byte;
-
- Procedure SetPal(Start: byte; Anz: word; pal: pointer); assembler;
- asm
- push ds
- cld
- lds si,pal
- mov dx,3c8h
- mov al,start
- out dx,al
- inc dx
- mov ax,anz
- mov cx,ax
- add cx,ax
- add cx,ax
- rep outsb
- pop ds
- end;
-
-
- Procedure GetPal(Start: byte; Anz: word; pal: pointer); assembler;
- asm
- les di,pal
- mov al,start
- mov dx,3c7h
- out dx,al
- inc dx
- mov ax,anz
- mov cx,ax
- add cx,ax
- add cx,ax
- mov dx,3c9h
- cld
- rep insb
- end;
-
-
- procedure GetFont; assembler; asm
- mov ax,1130h; mov bh,1; int 10h; mov Fseg,es; mov Fofs,bp; end;
-
- procedure SetGraphics(Mode : word); assembler;
- asm mov ax,Mode; int 10h; end;
-
- procedure Calcsinus(var SinTab : TabType); var I : byte; begin
- for I := 0 to 255 do SinTab[I] := round(sin(2*I*pi/255)*255); end;
-
- function Sinus(Idx : byte) : integer; begin
- Sinus := SinTab^[Idx]; end;
-
- function Cosinus(Idx : byte) : integer; begin
- Cosinus := SinTab^[(Idx+192) mod 255]; end;
-
- function keypressed : boolean; assembler;
- asm mov ah,0bh; int 21h; and al,0feh; end;
-
- Procedure DefineBlock;
- Var CounterX,
- CounterY : Word;
- Begin
- For CounterY := 0 to BlockMaxY-1 do
- For CounterX := 0 to BlockMaxX-1 do
- Block^[CounterY,CounterX]:=1+CounterX+(CounterY*BlockMaxX);
- End;
-
- Procedure DefinePalette;
- Var PalX : Byte;
- PalY : Byte;
- PalSize : Byte;
- I : Word;
- Const
- Imag : Array [0..BlockMaxY-1,0..BlockMaxX-1] OF Byte=
- ((0,0,0,0,0,0,7,7,7,7,0,0,0,0,0),
- (0,0,0,0,7,6,5,5,5,5,6,7,0,0,0),
- (0,0,0,7,5,4,4,3,3,3,3,5,7,0,0),
- (0,0,7,5,4,4,3,3,2,2,3,3,6,0,0),
- (0,0,6,5,4,4,3,2,1,1,2,3,4,7,0),
- (0,7,5,5,4,4,3,3,2,2,3,3,4,6,0),
- (0,7,5,5,4,4,4,3,3,3,3,4,4,6,0),
- (0,7,5,5,4,4,4,4,4,4,4,4,4,7,0),
- (0,0,6,5,5,4,4,4,4,4,4,4,5,7,0),
- (0,0,7,5,5,5,5,4,4,4,4,5,7,0,0),
- (0,0,0,7,5,5,5,5,5,5,5,7,0,0,0),
- (0,0,0,0,7,6,5,5,5,6,7,0,0,0,0),
- (0,0,0,0,0,0,0,0,0,0,0,0,0,0,0),
- (0,0,0,0,0,0,0,0,0,0,0,0,0,0,0));
-
- Begin
- PalSize := (BlockMaxX * BlockMaxY);
- For PalY:=0 to BlockMaxY-1 Do
- For PalX:=0 To BlockMaxX-1 Do
- With Blockpal^[(PalY*BlockMaxX)+PalX+1] do
- Case Imag[Paly,Palx] OF
- 0 : Begin R:= 0; G := 0; B:= 0; end;
- 1 : Begin R:= 5; G := 5; B:= 28; End;
- 2 : Begin R:= 1; G := 1; B:= 25; End;
- 3 : Begin R:= 1; G := 1; B:= 22; End;
- 4 : Begin R:= 1; G := 1; B:= 19; End;
- 5 : Begin R:= 1; G := 1; B:= 16; End;
- 6 : Begin R:= 1; G := 1; B:= 13; End;
- 7 : Begin R:= 1; G := 1; B:= 10; End;
- end;
- for I := 1 to 30 do
- With Blockpal^[I+210] do
- begin
- R:=64-Round((I-1)*1.8); G:=64-Round((i-1)*1.6); B:=0;
- end;
- for I := 1 to 8 do
- With Blockpal^[I+240] do
- begin
- R:=63-(I-1)*7; G:=53-(I-1)*7 ; B:=63-(I-1)*7;
- end;
- End;
-
- Procedure DrawScreen;
- var x,y,zz :Integer;
- begin
- For x:=0 to 319 do
- for y:=0 to 199 do
- IF Y<150 then
- VGA^[Y,X] :=Block^[Y MOD BlockMaxY, X MOD BlockMaxX]
- else
- VGA^[Y,X] :=Block^[(215-y) MOD BlockMaxY, (((X-160)*50
- DIV (y-100))+340+(Cosinus(y*20) div 150)) MOD BlockMaxX]
- end;
-
- {------ Routines for the "Moving Backround" -------}
-
- Procedure ShiftBackDown;
- Type TempPalType = Array[1..BlockMaxX] of PaletteRec;
- Var TempPal : TempPalType;
- CounterX,
- CounterY : Word;
- Begin
- For CounterX := 1 to BlockMaxX do
- TempPal[CounterX] := Blockpal^[CounterX];
- For CounterY := 0 to (BlockMaxY-1) do
- For CounterX := 0 to (BlockMaxX-1) do
- Blockpal^[1 + CounterX + (CounterY * BlockMaxX)] :=
- Blockpal^[1 + CounterX + ((CounterY+1) * BlockMaxX)];
- For CounterX := 1 to BlockMaxX do
- Blockpal^[CounterX + ((BlockMaxY-1) * BlockMaxX)] :=
- TempPal[CounterX];
- End;
-
- Procedure ShiftBackRight;
- Type TempPalType = Array[0..BlockMaxY-1] of PaletteRec;
- Var TempPal : TempPalType;
- CounterX,
- CounterY : Byte;
- Begin
- For CounterY := 0 to BlockMaxY-1 do
- TempPal[CounterY] := Blockpal^[1 + CounterY * BlockMaxX];
- For CounterX := 0 to BlockMaxX-1 do
- For CounterY := 0 to BlockMaxY-1 do
- Blockpal^[1 + (CounterY * BlockMaxX) + CounterX] :=
- Blockpal^[1 + (CounterY * BlockMaxX) + CounterX + 1];
- For CounterY := 0 to BlockMaxY-1 do
- Blockpal^[(CounterY * BlockMaxX) + BlockMaxX] := TempPal[CounterY];
- End;
-
- Procedure ShiftBackLeft;
- Type TempPalType = Array[0..BlockMaxY-1] of PaletteRec;
- Var TempPal : TempPalType;
- CounterX,
- CounterY : Word;
- Begin
- For CounterY := 0 to BlockMaxY-1 do
- TempPal[CounterY] := Blockpal^[(CounterY * BlockMaxX) + BlockMaxX];
- For CounterX := BlockMaxX-2 downto 0 do
- For CounterY := 0 to BlockMaxY-1 do
- Blockpal^[2 + (CounterY * BlockMaxX) + CounterX] :=
- Blockpal^[1 + (CounterY * BlockMaxX) + CounterX];
- For CounterY := 0 to BlockMaxY-1 do
- Blockpal^[1 + (CounterY * BlockMaxX)] := TempPal[CounterY];
- End;
- {--------------------------------------------------}
-
- Procedure CalcMorph(F,T,P : Byte);
- Var pnt,l,m : Byte;
- xd : shortInt;
- begin
- For pnt:=1 to NumPnts do
- For l:=1 to 3 do
- begin
- xd:=(Sxhmata^[T][pnt,l]-Sxhmata^[f][pnt,l]);
- MArr^[pnt,l]:=Sxhmata^[f][pnt,l]+((xd*p) DIV MorphSize);
- end;
- end;
-
- Procedure DoMorph;
- Type
- ShadePtsT = Array[1..NumPnts,0..2] OF Word;
- Var
- Shp : ShadePtsT;
- Frst,
- OutOfX,
- OutOfY : Boolean;
- sxhma,
- NSxhma,
- MPHase,
- Choice,DV,
- DTime,
- tempa : byte;
- Inv,iny,
- inz : Shortint; { Xstep , Ystep for Moving }
- I,
- X,Y,Z,
- X1,Y1,
- Z1,PhiX,
- PhiY,PhiZ : Integer;
- Count2,
- PalBuf : Word;
-
- begin
- Pa1:=@Sxhmata^[0];
- FillChar(Shp,SizeOF(SHp),0);
- FillChar(MArr^,SizeOF(MarrTyp),0);
- Sxhma:=0; PhiX := 0; PhiY := 0; PhiZ := 0;
- Inv:=2; iny:=-2; inz:=1;
- DTime := 100;
- Choice := 0;
- Frst:=True;
- Count2:=0; MPhase:=0;
- Move(VGA^[170,0],Cover,320*8);
- Repeat
- ShiftBackDown;
- If DTime=0
- Then
- Begin
- Choice := Random(3);
- DTime := 40 + Random(160);
- End;
- IF Choice=1 Then ShiftBackRight ELSE
- IF Choice=2 Then ShiftBackLeft;
- IF Dist=0 then inz:=2;
- IF Dist=200 then inz:=-2;
- DV:=Dist div 5;
- IF Count2>=150 then
- if (Sox>140) And (Sox<220) Then
- if (Soy>80) And (Soy<120) Then
- begin
- MPhase:=1;
- NSxhma:=Succ(Random(NumSxhma-1))+Sxhma;
- If NSxhma>=NumSxhma Then NSxhma:=NSxhma-NumSxhma;
- count2:=0;
- end;
- IF (MPhase>0) then
- IF Count2=2 Then
- IF (MPhase<MorphSize+1) Then
- begin
- CalcMorph(Sxhma,NSxhma,Mphase);
- Pa1:=@MArr^;
- Inc(MPhase);
- Count2:=0;
- end
- ELSE
- begin
- sxhma:=NSxhma;
- Pa1:=@Sxhmata^[Sxhma];
- Mphase:=0;
- end;
- Asm
- {--------- Rotate The Message ---------}
- mov ax,ds
- mov es,ax
- mov bl,8
- mov ax,OFFSET Txtbit
- mov di,ax
- Mov si,di
- inc si
- @RL1:
- mov al,[ds:di]
- mov cx,2048
- rep movsb
- mov [ds:di],al
- inc di
- inc si
- dec bl
- jnz @RL1
-
- {-------- Wait for V-Retrace ----------}
- mov dx,3dah;
- @lre1: in al,dx; test al,8; jnz @lre1;
- @lre2: in al,dx; test al,8; jz @lre2;
- {-------- Set Block Colors ---------}
- PUSH DS
- MOV CX, BlockMaxX * BlockMaxY * 3
- MOV AX, 1
- LDS SI, Blockpal
- INC SI
- INC SI
- INC SI
- MOV DX, 03C8h
- OUT DX, AL
- INC DX
- REP
- OUTSB
- POP DS
- {-------- Restore cover area ----------}
- mov di,320*170
- Mov es,Vseg
- mov si,OFFSET cover
- Mov cx,160*8
- @repem:
- Lodsw
- stosw
- dec cx
- jnz @repem
- {--------- Draw Message on screen ----------}
- mov di,320*170
- mov bl,8
- mov si,OFFSET Txtbit
- cld
- @l1:
- Mov cx,320
- @l3:
- lodsb
- cmp al,0
- je @l2
- stosb
- jmp @l4
- @l2: inc di
- @l4:
- dec cx
- jnz @l3
- MOV Ax,256*8-319
- add ax,si
- mov si,ax
- dec bl
- jnz @l1
- Mov OutOfX,0
- Mov OutOfY,0
- end;
- For i:=1 To NumPnts do
- begin
- asm
- Mov al,frst { IF (Not frst) AND (Lo(Shp[i,2])<211) then }
- cmp al,0 { Mem[Vseg:Shp[i,0]+320*Shp[i,1]]:=Lo(Shp[i,2]); }
- ja @skip
- Mov ax,i
- dec ax
- Shl ax,1
- mov si,ax
- Shl ax,1
- ADD si,ax
- mov ax,Word Ptr Shp[si+2]
- cmp ax, 200
- jae @skip
- mov bx,word ptr Shp[si]
- cmp bx,320
- jae @skip
- shl ax,6
- mov di,ax
- shl ax,2
- add di,ax
- add di,bx
- mov ax,Word Ptr Shp[si+4]
- cmp al,211
- jae @skip
- mov [es:di],al
- @Skip:
- end;
- X1 :=(Cosinus(PhiY)*Pa1^[I,1]-Sinus(PhiY)*Pa1^[I,3]) div 255;
- Y1 :=(Cosinus(PhiZ)*Pa1^[I,2]-Sinus(PhiZ)*X1) div 255;
- Z1 :=(Cosinus(PhiY)*Pa1^[I,3]+Sinus(PhiY)*Pa1^[I,1]) div 255;
- X := (Cosinus(PhiZ)*X1+Sinus(PhiZ)*Pa1^[I,2]) div (255+dist);
- Y := (Cosinus(PhiX)*Y1+Sinus(PhiX)*z1) div (255+dist);
- Z := (Cosinus(PhiX)*Z1-Sinus(PhiX)*Y1) div (255+dist);
- Shp[i,0] := Sox+((Xc*Z-X*Zc) div (Z-Zc));
- Shp[i,1] := soy+((Yc*Z-Y*Zc) div (Z-Zc));
- Shp[i,2]:=Mem[Vseg:Shp[i,0]+320*Shp[i,1]];
- IF Shp[i,0]>319 Then OutOfX:=True;
- IF Shp[i,1]>200-DV then OutOfY:=True;
- asm { Mem[Vseg:Shp[i,0]+320*Shp[i,1]]:= 240-((Z+40) DIV 3); }
- Mov ax,i
- dec ax
- Shl ax,1
- mov si,ax
- Shl ax,1
- ADD si,ax
- mov ax,Word Ptr Shp[si+2]
- cmp ax, 200
- jae @skip
- mov bx,word ptr Shp[si]
- cmp bx,320
- jae @skip
- shl ax,6
- mov di,ax
- shl ax,2
- add di,ax
- add di,bx
- Mov al,[es:di]
- cmp al,211
- jae @skip
- Mov ax,z
- add ax,40
- mov bl,3
- Div bl
- mov bl,240
- sub bl,al
- mov al,bl
- mov [es:di],al
- @skip:
- end;
- end;
- IF OutOfY Then IF SoY>100 Then INY:=-2 ELSE INY:=2;
- IF OutOfX Then IF SoX>160 Then INv:=-2 ELSE INv:=2;
- asm
- mov frst,0
- INC Phix; INC Phix; Inc Phiy; INC Phiz;
- Inc Count2; Dec DTime;
- end;
- Inc(Sox,inv);
- Inc(Soy,iny);
- Inc(Dist,Inz);
- Until Keypressed;
- end;
-
- Procedure MakeTxtBit;
- var
- i,l,x,CH : BYTE;
- begin
- Fillchar(TxtBit,SizeOF(TxtBit),0);
- For i:=0 to Length(scrtext)-1 Do
- begin
- Ch := ord(ScrText[I+1]);
- For L:=0 to 7 do
- for x:=0 to 7 do
- IF ((Mem[Fseg:Fofs+8*ch+l] Shl X) AND 128)<>0 then
- TxtBit[l,(i*8)+x]:=241+(L);
- end;
- end;
-
- Procedure SxhmataProc; External;
- {$L Sxhmata.obj}
-
- begin
- New(Sintab);
- New(Marr);
- New(BlockPal);
- New(Block);
- CalcSinus(Sintab^);
- Getfont;
- MakeTxtBit;
- Sxhmata:=@SxhmataProc;
- Randomize;
- VGA := Ptr($A000,$0000);
- SetGraphics($13);
- DefineBlock;
- Fillchar(BlockPal^,SizeOF(BlockPal^),0);
- SetPal(0,255,BlockPal);
- DrawScreen;
- DefinePalette;
- SetPal(0,255,BlockPal);
- DoMorph;
- { Dispose(Block);Dispose(BlockPal);Dispose(Marr);Dispose(SinTab); }
- { Not Needed since TP disposes all of theese by itself on exit }
- SetGraphics(3);
- For i:=1 to 7 Do WriteLN(FinText[i]);
- asm
- int 16h
- cmp al,0
- jz @fin
- int 16h
- @fin:
- end;
- end.